home *** CD-ROM | disk | FTP | other *** search
/ CD ROM Paradise Collection 4 / CD ROM Paradise Collection 4 1995 Nov.iso / graphics / vgafx.zip / FLASH1.ASM < prev    next >
Assembly Source File  |  1989-11-03  |  29KB  |  841 lines

  1. Comment |
  2.  
  3.     This module demonstrates special effect attributes in attribute
  4.     control mode 1 and provides several user-callable functions for
  5.     attribute manipulation.  The callable functions are:
  6.  
  7.       flash_init          Initializes system; call before using others
  8.       flash_term          Restores system; call before terminating
  9.       set_flash_rate      Sets number of timer ticks between palettes
  10.       set_delta           Sets number added to current palette per change
  11.       load_palettes       Loads all 16 palettes into VGA
  12.       reset_palettes      Resets to 16 base palettes
  13.       pulse_color         Creates a pulsing color, 16 palettes
  14.       pulse_color_partial Creates a pulsing color, < 16 palettes
  15.       set_color           Defines a color for one attibute, all 16 palettes
  16.       set_color_partial   Defines a color for one attibute, < 16 palettes
  17.       grade_color         Creates a graded color over 16 palettes
  18.       grade_color_partial Creates a grade color over < 16 palettes
  19.       blinker             Copies BG colors into FG, for simulated blinking
  20.  
  21.     Additionally, one data item is public to the user.  FLASH_ENABLED
  22.     is a byte variable; a zero value here disables palette changes,
  23.     effectively "freezing" the colors currently displayed.
  24.  
  25.     The module is designed for linking into a COM program.  All functions
  26.     are NEAR calls and assume DS=ES, except for TIMER_INT, which is an
  27.     interrupt intercept and assumes that CS=DS=ES.
  28.  
  29.     The module prologues provide greater detail on function requirements
  30.     and register use.
  31.  
  32.     Tested under MASM 5.1 and OPTASM 1.5.
  33.  
  34.     Prep:
  35.         masm flash0;
  36.            -or-
  37.         optasm flash0;
  38.         link hostprog+flash0;
  39.         exe2bin hostprog
  40.  
  41.     Uncopyrighted material, use freely
  42.     By Chris Dunford/Cove Software (CompuServe 76703,2002; tel. 301/992-9371)
  43.  
  44.     Version history:
  45.         1.00 10/09/89
  46.  
  47. |
  48.  
  49. public flash_init,flash_term
  50. public pulse_color,pulse_color_partial
  51. public grade_color,grade_color_partial
  52. public set_color,set_color_partial
  53. public blinker
  54. public load_palettes,reset_palettes
  55. public set_flash_rate,set_delta
  56. public flash_enabled
  57.  
  58. ; This equate determines whether TIMER_INT uses BIOS or register-level
  59. ; programming to accomplish palette changes.  Set to 0 for register-level,
  60. ; any non-zero value for BIOS level.
  61. USE_BIOS equ 0
  62.  
  63. ; Macro accesses the palette control video BIOS function (fn 10H)
  64. ; Call: palctrl subfunction
  65. palctrl macro fn
  66.         mov ax,10h shl 8 + fn
  67.         int 10h
  68. endm
  69.  
  70. ; Structure for storing graded color scaling data.  See CALC_SCALE_FACTORS.
  71. scale_factors struc
  72. incr        db ?
  73. xs_count    db ?
  74. xs_incr_val db ?
  75. scale_factors ends
  76.  
  77. ; Subfunctions (AL values) for palette control function
  78. _SET_PALREGS           equ 2
  79. _GET_PALREGS           equ 9
  80. _SET_COLOR             equ 10h
  81. _SET_DACS              equ 12h
  82. _SET_ATR_SELECT_STATE  equ 13h
  83. _GET_DACS              equ 17h
  84. _GET_ATR_SELECT_STATE  equ 1AH
  85.  
  86.  
  87. code segment word public 'code'
  88. assume cs:code,ds:code,es:code
  89.  
  90. ; ========================================================================
  91. ;                          DATA FOR VGA MANIPULATION
  92. ; ========================================================================
  93.  
  94. ; Storage for the original 16 palettes
  95. origpals db 16*16*3 dup (0)     ; 16 palettes, 16 colors each, 3 RGB values per
  96.  
  97. ; Additional saved state info
  98. orig_mode           db ?                ; Original attr control mode
  99. orig_color_select   db ?                ; Original color select reg value
  100.  
  101. ; Storage for the augmented palettes
  102. newpals  db 16*16*3 dup (0)
  103.  
  104. ; Storage for the 16 palatte registers + overscan reg
  105. palregs db 17 dup (0)
  106.  
  107. ; The 16 new palette register contents we will use, plus overscan
  108. newpalregs db 0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,0
  109.  
  110. ; Storage for factors used to scale one color to another over
  111. ; fifteen palettes.  Don't separate or re-order; module assumes
  112. ; that the R/G/B records are contiguous and in that order.
  113. red_scale   scale_factors <>
  114. green_scale scale_factors <>
  115. blue_scale  scale_factors <>
  116.  
  117. ; Color definitions for our 16 base colors.  16 colors, 3 RGB values each
  118. new_base_pal label byte
  119. .radix 16
  120.         db 00,00,00    ; Color 0 (normally black)
  121.         db 00,00,2A    ; Color 1 (blue)
  122.         db 00,2A,00    ; Color 2 (green)
  123.         db 00,2A,2A    ; Color 3 (cyan)
  124.         db 2A,00,00    ; Color 4 (red)
  125.         db 2A,00,2A    ; Color 5 (magenta)
  126.         db 2A,2A,00    ; Color 6 (brown)
  127.         db 2A,2A,2A    ; Color 7 (white)
  128.  
  129.         db 00,00,15    ; Color 8 (some very dark color)
  130.         db 00,00,33    ; Color 9 (brt blue)
  131.         db 00,33,00    ; Color 10 (brt green)
  132.         db 00,33,33    ; Color 11 (brt cyan)
  133.         db 33,00,00    ; Color 12 (brt red)
  134.         db 33,00,33    ; Color 13 (brt magenta)
  135.         db 33,33,00    ; Color 14 (yellow)
  136.         db 33,33,33    ; Color 15 (brt white)
  137. .radix 10
  138.  
  139. ; Flasher data
  140. flash_enabled       db 1                ; 0=disabled, 1=enabled
  141. flash_reset_count   dw 1                ; Flash rate, in timer ticks
  142. count               dw 9                ; Remaining countdown
  143. pal_select          db 0                ; Current palette #
  144. delta               db 1                ; # palettes to change per flash
  145.  
  146. ; Storage for original timer vector
  147. oldtimer label dword
  148. tickvec_lo dw ?
  149. tickvec_hi dw ?
  150.  
  151. ; ========================================================================
  152. ;                              CALLABLE FUNCTIONS
  153. ; ========================================================================
  154.  
  155.  
  156. ; ----- flash_init ------------------------------------------------------
  157. ; This function must be called to initialize the system for controlled
  158. ; flashing.  It accomplishes several tasks:
  159. ;
  160. ;    - Saves the 16 palette registers in palregs
  161. ;    - Gets the current 256 colors (4 palettes) to origpals
  162. ;    - Duplicates palette 0 in palette 1 and loads it into the VGA
  163. ;    - Installs the timer intercept
  164. ;
  165. ; On exit, flashing is set up, but nothing is actually flashing (because
  166. ; palettes 0 and 1 are identical).
  167. ;
  168. ; Returns CF=1 if no VGA detected.  All regs except segregs may be destroyed.
  169. ;
  170. flash_init:
  171.  
  172. ; Make sure we've got a VGA.  Use a VGA-only function, and one that
  173. ; we can use to save the current attribute control mode and color select reg.
  174.         palctrl _GET_ATR_SELECT_STATE   ; A VGA-only function
  175.         mov orig_mode,bl
  176.         mov orig_color_select,bh
  177.         cmp al,_GET_ATR_SELECT_STATE
  178. ;        jne got_VGA
  179. ;            stc                         ; Oops
  180. ;            jmp fi_exit
  181.  
  182. ; Save the 16 current palette registers into palregs; reset the
  183. ; palette registers to contain 16 "standard" 4-bit colors.
  184. got_VGA:
  185.         ; Get current regs
  186.         mov dx,offset palregs
  187.         palctrl _GET_palregs
  188.  
  189.         ; Continue to use the current border color
  190.         mov al,palregs+16
  191.         and al,0FH
  192.         mov newpalregs+16,al
  193.  
  194.         ; Set new palregs
  195.         mov dx,offset newpalregs
  196.         palctrl _SET_PALREGS
  197.  
  198. ; Save the original DAC color registers (256 colors) in origpals
  199.         xor bx,bx                       ; Start with register 0
  200.         mov cx,256                      ; 256 registers
  201.         mov dx,offset origpals          ; Where to put 'em
  202.         palctrl _GET_DACS
  203.  
  204. ; Create 16 standard palettes in newpals and send them to the VGA
  205.         call dupe_palette0
  206.         mov dx,offset newpals
  207.         call set_colors
  208.  
  209. ; Set attribute control mode 1
  210.         mov bx,100h
  211.         palctrl _SET_ATR_SELECT_STATE
  212.  
  213. ; Save/set the timer intercept
  214.         push es
  215.         mov ax,3508h
  216.         int 21h
  217.         mov tickvec_lo,bx
  218.         mov tickvec_hi,es
  219.         pop es
  220.  
  221.         mov dx,offset timer_int
  222.         mov ax,2508h
  223.         int 21h
  224.  
  225.         clc
  226.  
  227. fi_exit:
  228.         ret
  229.  
  230. ; ----- flash_term -----------------------------------------------------
  231. ; This function must be called for cleanup when program terminates:
  232. ;    - Deactivates the timer intercept
  233. ;    - Restores the original VGA state
  234. ; AX,BX,CX,DX destroyed
  235. ;
  236. flash_term:
  237.  
  238. ; Clear the timer interrupt
  239.         push ds
  240.         lds dx,oldtimer
  241.         mov ax,2508h
  242.         int 21h
  243.         pop ds
  244.  
  245. ; Restore original palette registers and video DAC color registers
  246.         mov dx,offset palregs
  247.         palctrl _SET_PALREGS
  248.         mov dx,offset origpals
  249.         call set_colors
  250.  
  251. ; Restore original attribute control mode
  252.         xor bl,bl                       ; Subfn to set control mode
  253.         mov bh,orig_mode
  254.         palctrl _SET_ATR_SELECT_STATE
  255.  
  256. ; Go back to palette 0
  257.         mov bl,1                        ; Subfn to set color select reg
  258.         mov bh,orig_color_select        ; Value to set
  259.         palctrl _SET_ATR_SELECT_STATE
  260.  
  261.         ret
  262.  
  263. ; ----- set_flash_rate ------------------------------------------------
  264. ; Reset the flash rate to the number of ticks in AX (18/sec); i.e.,
  265. ; the palette will change every AX ticks.  All regs preserved.
  266. ;
  267. set_flash_rate:
  268.         cli
  269.         mov flash_reset_count,ax
  270.         mov count,ax
  271.         sti
  272.         ret
  273.  
  274. ; ----- set_delta ------------------------------------------------------
  275. ; Set the increment value for palette changes.  When the ticker
  276. ; ticks down and the palette is to be changed, the timer ISR will
  277. ; add/subtract this number to the current palette number.  With a
  278. ; higher delta, you can flash more rapidly.  E.g., with delta=1,
  279. ; the palettes change 0,1,2,3,...,15.  With delta=3, the palette
  280. ; changes are 1,3,6,9,12,15.  If delta=0, only palette 0 is used.
  281. ;
  282. ; AX destroyed.
  283. ;
  284. set_delta:
  285.         push cx
  286.         and al,15
  287.         mov cl,al
  288.         cli
  289.         mov delta,al
  290.  
  291.         ; Ensure that the selected palettes will
  292.         ; be multiples of the delta
  293.         or cl,cl
  294.         jnz SD20
  295.             xor al,al
  296.             jmp SD50
  297.  
  298. SD20:
  299.             mov al,pal_select
  300.             xor ah,ah
  301.             div cl
  302.             mul cl
  303.  
  304. SD50:
  305.         mov pal_select,al
  306.         sti
  307.         pop cx
  308.         ret
  309.  
  310. ; ----- load_palettes -------------------------------------------------
  311. ; Load the set of palettes in NEWPALS into the VGA.
  312. ;
  313. load_palettes:
  314.         mov dx,offset newpals
  315.         call set_colors
  316.         ret
  317.  
  318. ; ----- reset_palettes ----------------------------------------------
  319. ; This function resets the VGA to 16 copies of the "standard" palette.
  320. ;
  321. reset_palettes:
  322.         call dupe_palette0
  323.         call load_palettes
  324.         ret
  325.  
  326. ; ----- pulse_color_partial ----------------------------------------
  327. ; Creates a "pulsing" attribute.  This is one whose intensity increases
  328. ; and decreases cyclically.  On entry:
  329. ;    AL = attribute
  330. ;    AH = intensity increase/palette (each palette's RGB values
  331. ;         will be this much higher than the previous palette's)
  332. ;    CH = base palette
  333. ;    CL = terminal palette
  334. ; The color definition in palette CH is unaffected; palettes CH+1..CL
  335. ; will contain augmented color definitions.  Function does nothing
  336. ; if CL >= CH.
  337. ;
  338. ; AX destroyed.  New palettes not loaded into VGA.
  339. ;
  340. pulse_color_partial:
  341.  
  342.         push bx
  343.         push cx
  344.         push si
  345.         push di
  346.  
  347. ; Verify the palette numbers
  348.         cmp ch,15                       ; CH > 15?
  349.         ja P90                          ; Yes
  350.         cmp cl,ch                       ; CL >= CH?
  351.         jae P90                         ; Yes
  352.  
  353. ; Address the base definition (palette CL) for this attribute
  354.         call get_DAC_ptr
  355.         mov si,bx                       ; SI -> first definition
  356.         sub ch,cl                       ; CH = # of palettes affected
  357.         mov cl,ch
  358.         xor ch,ch                       ; Now CX
  359.  
  360.  
  361. ; Loop through the required number of palettes
  362. p_palette_loop:
  363.             push cx
  364.             mov cx,3
  365.             mov di,si                   ; SI/DI -> color def, crnt palette
  366.             add di,16*3                 ; DI -> color def, next palette
  367. p_RGB_loop:
  368.                 lodsb                   ; Get R/G/B intensity, crnt pal
  369.                 or al,al                ; Don't increment missing primaries
  370.                 jz P10
  371.                     add al,ah           ; Add per-palette increment
  372.                     cmp al,63           ; Don't let it go past 63
  373.                     jbe P10
  374.                     mov al,63
  375. P10:            stosb                   ; Store increment value in next pal
  376.                 loop p_RGB_loop         ; Loop for 3 primaries
  377.             pop cx
  378.             add si,16*3-3               ; Next palette
  379.         loop p_palette_loop
  380.  
  381. P90:
  382.         pop di
  383.         pop si
  384.         pop cx
  385.         pop bx
  386.         ret
  387.  
  388. ; ----- pulse_color -----------------------------------------------------
  389. ; Identical to pulse_color_partial except that a full range 0-15 is used;
  390. ; reg CX input not required.
  391. ;
  392. ; Entry: see pulse_color_partial; CH/CL not required.
  393. ;
  394. ; AX destroyed.  New palettes not loaded into VGA.
  395. ;
  396. pulse_color:
  397.  
  398.         push cx
  399.         mov cx,0F00H
  400.         call pulse_color_partial
  401.         pop cx
  402.         ret
  403.  
  404.  
  405. ; ----- set_color_partial --------------------------------------------
  406. ; This function sets the color definitions for attribute AL in palettes
  407. ; CL to CH to the 3-byte RGB definition at DS:SI.  Ensure that CH >= CL
  408. ; and that both are in the range 0..15.  The new palette is not sent to
  409. ; the VGA.
  410. ;
  411. ; The function does nothing if CL > CH or either is not in the range
  412. ; 0-15.
  413. ;
  414. ; AX destroyed.
  415. ;
  416. set_color_partial:
  417.  
  418.         push bx
  419.         push cx
  420.         push si
  421.         push di
  422.  
  423. ; Verify the palette numbers
  424.         cmp ch,15                       ; CH > 15?
  425.         ja S10                          ; Yes
  426.         cmp cl,ch                       ; CL >= CH?
  427.         ja S10                          ; Yes
  428.  
  429. ; Address the base definition (palette CL) for this attribute
  430.         call get_DAC_ptr
  431.         mov di,bx                       ; DI -> first definition
  432.         inc ch
  433.         sub ch,cl                       ; CH = # of palettes affected
  434.         mov cl,ch
  435.         xor ch,ch                       ; Now CX
  436.  
  437. ; Loop through the required number of palettes
  438. sc_palette_loop:
  439.             push si                     ; Copy def from SI to palette n
  440.             lodsb
  441.             stosb
  442.             lodsw
  443.             stosw
  444.             pop si
  445.             add di,16*3-3               ; DI -> color def in pal n+1
  446.         loop sc_palette_loop
  447.  
  448. S10:
  449.         pop di
  450.         pop si
  451.         pop cx
  452.         pop bx
  453.         ret
  454.  
  455. ; ----- set_color --------------------------------------------------
  456. ; Identical to set_color_partial, except that the full range of
  457. ; palettes (0..15) is assumed.  I.e., this function defines all palettes
  458. ; for attribute AL to contain the RGB color definition at DS:SI.
  459. ; Reg CX input not required.
  460. ;
  461. set_color:
  462.         push cx
  463.         mov cx,0F00h
  464.         call set_color_partial
  465.         pop cx
  466.         ret
  467.  
  468. ; ----- grade_color_partial ------------------------------------------
  469. ; This function creates a graded set of colors for attribute AL.
  470. ; CL contains a starting palette (0-14) and CH contains an ending
  471. ; palette (1-15, CH > CL).
  472. ;
  473. ; DS:SI points to the "terminal" color definition, which will be
  474. ; the definition in palette CH.  On exit, palettes CL-CH will contain
  475. ; "graded" color definitions for the attribute, so that the displayed
  476. ; color will change slowly from the base color (in palette CL) to the
  477. ; terminal color (in palette CH).  The color definition at DS:SI
  478. ; is three bytes long (one byte each for R, G, B intensity).  RGB
  479. ; values are modulated into the range 0-63.  The new palette is not
  480. ; sent to the VGA.  AX destroyed.
  481. ;
  482. ; The function does nothing if CL >= CH or either is not in the range
  483. ; 0-15.
  484. ;
  485. grade_color_partial:
  486.  
  487.         push bx
  488.         push cx
  489.         push si
  490.         push di
  491.  
  492. ; Verify the palette numbers
  493.         cmp ch,15                       ; CH > 15?
  494.         ja G10                          ; Yes
  495.         cmp cl,ch                       ; CL >= CH?
  496.         jae G10                         ; Yes
  497.  
  498. ; Address the base definition (palette CL) for this color
  499.         call get_DAC_ptr
  500.         push bx
  501.         sub ch,cl                       ; CH = # of palettes graded
  502.         mov cl,ch
  503.         xor ch,ch                       ; Now CX
  504.         mov di,offset red_scale
  505.         call calc_scale_factors         ; Calc red scaling factors
  506.         call calc_scale_factors         ;  "   grn   "       "
  507.         call calc_scale_factors         ;  "   blue  "       "
  508.         pop si                          ; SI -> initial definition
  509.  
  510. ; Loop through the required number of palettes
  511. gc_palette_loop:
  512.             mov di,si                   ; SI/DI -> color def in palette n
  513.             add di,16*3                 ; DI -> color def in pal n+1
  514.  
  515.             ; Augment RGB values for this video DAC color register
  516.             mov bx,offset red_scale     ; Point to red scale factors
  517.             call increment              ; Scale red
  518.             call increment              ; Scale green
  519.             call increment              ; Scale blue
  520.  
  521.             add si,16*3-3               ; Next palette
  522.             loop gc_palette_loop
  523.  
  524. G10:
  525.         pop di
  526.         pop si
  527.         pop cx
  528.         pop bx
  529.         ret
  530.  
  531. ; ----- grade_color --------------------------------------------------
  532. ; This is the same as GRADE_COLOR_PARTIAL, except that a full 15-palette
  533. ; grade is automatic.  Reg CX input is not required.
  534. ;
  535.  
  536. grade_color:
  537.         push cx
  538.         mov cx,0F00h                    ; Grade palettes 0-15
  539.         call grade_color_partial
  540.         pop cx
  541.         ret
  542.  
  543. ; ----- blinker --------------------------------------------------
  544. ; This function creates a simulated "blinking" color for attribute
  545. ; AL.  Unlike most of the other functions, this one works with a
  546. ; full 8-bit attribute (bits 0-3=FG, 4-7=BG, as usual).  "Blinking"
  547. ; is accomplished by putting the BG color definition into palettes
  548. ; 8-15 for the selected FG color.
  549. ;
  550. ; Note that palettes 0-7 are not altered, so you can do whatever
  551. ; you want with the "visible" half of the blink text (like scaling it,
  552. ; as is done in the "softened blinking" demo.
  553. ;
  554. ; AX destroyed.  New palette not sent to VGA.
  555. ;
  556. blinker:
  557.         push bx
  558.         push cx
  559.  
  560. ; Get a pointer to the color definition for the BG attribute
  561.         push ax
  562.         mov cl,4                        ; Mov high nibble (BG) to low
  563.         shr al,cl
  564.         xor cl,cl                       ; Get ptr to def in palette 0
  565.         call get_DAC_ptr
  566.         mov si,bx                       ; SI->BG def, palette 0
  567.         pop ax
  568.  
  569. ; Now do a SET_COLOR for the FG attribute in palettes 8-15,
  570. ; using the color definition at DS:SI (which is the BG color)
  571.         and al,0FH                      ; Mask the BG attribute number
  572.         mov cx,0F08h                    ; Palettes 8-15
  573.         call set_color_partial
  574.  
  575.         pop cx
  576.         pop bx
  577.         ret
  578.  
  579. ; =======================================================================
  580. ;                             INTERNAL SUBROUTINES
  581. ; =======================================================================
  582.  
  583. ; ----- dupe_palette0 -----------------------------------------------
  584. ; This function creates 16 "standard" palettes in NEWPALS.
  585. ; The palettes are not loaded into the VGA.
  586. ; Regs used: AX,CX,SI,DI
  587. ;
  588. dupe_palette0:
  589.         ; Copy the base palette into palette 0 of newpals.  Each color
  590.         ; register contains 3 colors (R, G, and B), so the full palette
  591.         ; is 16*3 bytes long
  592.         mov si,offset new_base_pal
  593.         mov di,offset newpals
  594.         mov cx,16*3/2                  ; 256 colors, 3 RGB values each
  595.         cld
  596.         rep movsw
  597.  
  598.         ; Now duplicate pallete 0 (colors 0-15) to pals 1-15 (colors 16-255)
  599.         ; We simplify this by allowing the copies to overlap.
  600.         mov si,offset newpals           ; SI -> palette 0
  601.         mov di,offset newpals+16*3      ; DI -> palette 1
  602.         mov cx,15*16*3/2                ; 15 pals, 16 colors each, @ 3 bytes
  603.         rep movsw
  604.  
  605.         ret
  606.  
  607.  
  608. ; ----- calc_scale_factors ---------------------------------------------
  609. ; This function generates the parameters for scaling a color from
  610. ; an initial value to a terminal value.  On entry, DS:BX points
  611. ; to an initial color value (0-63), DS:SI points to a terminal
  612. ; color value (0-63), and ES:DI points to a 3-byte interpolation
  613. ; factor storage area.  The function calculates the numbers needed
  614. ; to scale the color from the initial definition to the terminal
  615. ; definition over a span of CL palettes (normally 15).
  616. ;
  617. ; The 3-byte factor storage area is filled as follows:
  618. ;       byte signed integer: increment/palette
  619. ;       byte unsigned integer: number of extra increments required
  620. ;       byte signed integer: excess increment value (1 or -1)
  621. ;
  622. ; To scale a palette, start with palette 0 and add the increment/palette
  623. ; to each succeeding palette.  Also add the excess increment value (1 or -1)
  624. ; to the first n palettes (1-n), where n is the number of extra increments.
  625. ; For example, if the initial color value is 21 and the terminal is 63, the
  626. ; factor storage area would contain 2,12,1.  To scale from 21 to 63, start
  627. ; with the value in palette 0 and add 3 per palette (2+1) from 1-12 and two
  628. ; per palette from 13-15:
  629. ;       0  1  2  3  4  5  6  7  8  9  10 11 12 13 14 15
  630. ;       21 24 27 30 33 36 39 42 45 48 51 54 57 59 61 63
  631. ; (Everything in the above assumes a 15-palette scale).
  632. ;
  633. ; On exit, BX and SI have been incremented by one, and DI by 3.  This
  634. ; conveniently points to the next color values and factor storage area.
  635. ; Other regs are preserved.
  636. ;
  637. calc_scale_factors:
  638.  
  639. ; Make sure CL is OK
  640.         and cl,0FH
  641.         or cl,cl
  642.         jnz CSF10
  643.           mov cl,15
  644. CSF10:
  645.  
  646. ; Get the initial color to AH and terminal color to AL
  647.         mov al,[bx]                     ; Initial color value
  648.         inc bx
  649.         mov ah,al
  650.         lodsb                           ; Terminal color value
  651.         and al,3FH                      ; Force 0-63
  652.  
  653. ; Compute increment/palette and number of excess increments needed
  654.         sub al,ah                       ; AL = difference (term-init)
  655.         cbw
  656.         idiv cl                         ; AL = inc/pal, AL = excess
  657.         mov [di.incr],al                ; Store increment/palette
  658.  
  659. ; Decide whether the excess increment value is +1 or -1.  It will be
  660. ; -1 if the "excess" calculated above is negative; the excess count will
  661. ; also have to be made positive, if so.
  662.         mov al,1                        ; Assume positive
  663.         or ah,ah                        ; Is it negative?
  664.         jns I1                          ; No, continue
  665.           neg al                        ; Yes, make increment negative
  666.           neg ah                        ; And count positive
  667. I1:     mov [di.xs_count],ah            ; Store the values
  668.         mov [di.xs_incr_val],al
  669.         add di,type scale_factors       ; Next storage area
  670.  
  671.         ret
  672.  
  673. ; ----- increment -----------------------------------------------------
  674. ; This subfunction increments a color value from palette n to palette
  675. ; n+1 using the scale factors at DS:BX (see CALC_SCALE_FACTORS).
  676. ; Entry: DS:BX->scale factors, DS:SI->palette n color value,
  677. ; ES:DI -> palette n+1 color value.  On exit, SI has been incremented
  678. ; (to point to the next color value), and BX is increased by 3 (to point
  679. ; to the next scale factor storage area).  The xs_incr field of the
  680. ; scale factor record is decremented if not already zero.
  681. ;
  682. increment:
  683.             lodsb                       ; Get original R/G/B value
  684.             add al,[bx.incr]            ; Add per-palette increment
  685.             test [bx.xs_count],-1       ; Any excess increments left?
  686.             jz no_rem                   ; No
  687.               dec [bx.xs_count]         ; Yes, dec remaining excess count
  688.               add al,[bx.xs_incr_val]   ; And add the excess incrmt (1/-1)
  689. no_rem:
  690.             stosb                       ; Store the graded value
  691.             add bx,type scale_factors
  692.             ret
  693.  
  694. ; ----- set_colors --------------------------------------------------
  695. ; This function sets the 256 video DAC color registers from the table
  696. ; at ES:DX, i.e., it loads the 256 colors definitions into the VGA.
  697. ;
  698. set_colors:
  699.         push ax
  700.         push bx
  701.         push cx
  702.         xor bx,bx                       ; Start with register 0
  703.         mov cx,256                      ; 256 colors
  704.         palctrl _SET_DACS
  705.         pop cx
  706.         pop bx
  707.         pop ax
  708.         ret
  709.  
  710.  
  711. ; ----- get_DAC_ptr ----------------------------------------------
  712. ; Returns a pointer in BX to the color definition for attribute AL
  713. ; in palette CL of NEWPALS.  Other regs preserved.
  714. ;
  715. get_DAC_ptr:
  716.         push ax
  717.         and ax,0FH                      ; Ensure range 0-15
  718.         mov bx,ax
  719.         mov al,newpalregs[bx]           ; Get palreg for this attrib
  720.         mov bx,ax                       ; Triple it for offset into color tab
  721.         shl bx,1
  722.         add bx,ax                       ; BX = 3 * color #
  723.         mov al,16*3                     ; Bytes/palette
  724.         mul cl                          ; AX -> offset of palette CL
  725.         add bx,ax                       ; BX -> offset of color def in NEWPALS
  726.         add bx,offset newpals           ; BX -> base color definition
  727.         pop ax
  728.         ret
  729.  
  730. ; =======================================================================
  731. ;                               TIMER INTERCEPT
  732. ; =======================================================================
  733.  
  734. Comment |
  735.   This is the timer intercept.  On each timer tick, we decrement the
  736.   countdown (if we are enabled).  If the count goes to zero, we go to
  737.   the next palette.  The next palette is determined by the current
  738.   palette (in pal_select) and the delta value; delta is added to
  739.   the current value and range checked.  If the new palette is out of
  740.   range, it's brought in range and the sign of delta is changed.
  741. |
  742.  
  743. timer_int:
  744.         assume cs:code,ds:nothing,es:nothing
  745.  
  746. ; Is the flasher enabled?
  747.         test flash_enabled,-1
  748.         jz timer9                       ; No
  749.  
  750. ; Dec count, skip rest if nonzero
  751.         dec count
  752.         jnz timer9
  753.  
  754. ; Count has zeroed, switch palettes by adding the delta.  If the
  755. ; palette number goes out of range, reverse the sign of the delta
  756. ; and bring the palette number back into range.  PAL_SELECT has
  757. ; the current palette number.
  758.         push ax
  759.         push bx
  760.  
  761.         mov bh,pal_select               ; Get current palette
  762.  
  763.         add bh,delta                    ; Add the delta
  764.         js P2                           ; Go if new palette not negative
  765.  
  766. P1:     cmp bh,15                       ; Check for positive out-of-range
  767.         jbe pal_OK                      ; It's OK
  768. P2:       neg delta                     ; Reverse the direction
  769.           add bh,delta
  770.           add bh,delta
  771.  
  772. pal_OK:
  773.         mov pal_select,bh               ; Save new palette
  774. if USE_BIOS
  775. ; Use BIOS to set color select register (palette)
  776.         mov bl,1                        ; And send it to the VGA
  777.         palctrl _SET_ATR_SELECT_STATE
  778. else
  779. ; Use register-level programming of the attribute control reg (ACR)
  780.         push dx
  781.  
  782.         ; Get port address of CRT status register
  783.         xor ax,ax
  784.         push ds
  785.         mov ds,ax
  786.         mov dx,ds:[463h]                ; DX = 3x8 register
  787.         pop ds
  788.         add dx,6                        ; DX = 3xA, CRT status reg
  789.  
  790.         ; Wait for a retrace
  791.         push cx
  792.         mov ah,5
  793.         xor cx,cx
  794. t_wait:     in al,dx
  795.             test al,8
  796.             jnz t_go
  797.             loop t_wait
  798.             dec ah
  799.             jnz t_wait
  800. t_go:   pop cx
  801.  
  802.         ; Do rest with ints off
  803.         pushf
  804.         cli
  805.  
  806.         ; Set color select
  807.         in al,dx                        ; Set addr/data flipflop in ACR
  808.         push dx                         ; Save CRT status reg port #
  809.  
  810.         mov dx,3C0H                     ; Select ACR reg 14h (color select)
  811.         mov al,14h
  812.         out dx,al
  813.         jmp $+2
  814.  
  815.         mov al,bh                       ; Send color select data
  816.         out dx,al
  817.  
  818.         pop dx                          ; Recover CRT status reg
  819.         in al,dx                        ; Reset flipflop
  820.         mov dx,3C0h                     ; ACR again
  821.         mov al,20h                      ; Restore palette
  822.         out dx,al
  823.  
  824.         popf                            ; Ints back on
  825.  
  826.         pop dx
  827. endif
  828.  
  829.         mov ax,flash_reset_count        ; Reset the count
  830.         mov count,ax
  831.  
  832.         pop bx
  833.         pop ax
  834.  
  835. ; Done, go do the real timer routine
  836. timer9:
  837.         jmp oldtimer
  838.  
  839. code ends
  840. end
  841.